TableCountRows Function

private function TableCountRows(lines) result(rows)

Count the number of rowss in a table stored in a collection of lines. Method: count the number of non blank lines that have not a keyword. Arguments: lines collections of lines Result: Return number of rows

Arguments

Type IntentOptional Attributes Name
character(len=LINELENGTH), intent(in), POINTER :: lines(:)

Return Value integer(kind=short)


Variables

Type Visibility Attributes Name Initial
character(len=300), public :: before
integer(kind=short), public :: i
character(len=LINELENGTH), public :: string

Source Code

FUNCTION TableCountRows &
  ( lines )             &
RESULT (rows)

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringToUpper, StringSplit

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)

! Local scalars:
INTEGER (KIND = short) :: rows 
INTEGER (KIND = short) :: i
CHARACTER (LEN = LINELENGTH)  :: string
CHARACTER (LEN = 300)  :: before
!------------end of declaration------------------------------------------------

string = ''
rows = 0

! scan table to count lines that have not a keyword.
DO i = 1, SIZE (lines)
  string =  lines (i)
  CALL StringSplit ( ':', string, before)
  
  IF ( StringToUpper ( before(1:5)) == "TITLE"        .OR. &
       StringToUpper ( before(1:2)) == "ID"           .OR. &
       StringToUpper ( before(1:5)) == "UNITS"        .OR. &
       StringToUpper ( before(1:7)) == "COLUMNS"      .OR. &
       StringToUpper ( before(1:11)) == "TABLE START" .OR. &
       StringToUpper ( before(1:9)) == "TABLE END") THEN 
    ! this is a line with a keyword not a row of table
  ELSE
    rows = rows + 1
  END IF
END DO

END FUNCTION TableCountRows